ReadMetadataFileName Subroutine

private subroutine ReadMetadataFileName(filename, network)

read metadata section from file

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
type(ObservationalNetwork), intent(out) :: network

Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: err_io
integer(kind=short), public :: fileunit
integer(kind=short), public :: i
type(IniList), public :: ini
character(len=300), public :: string

Source Code

SUBROUTINE ReadMetadataFileName &
!
(filename, network)

IMPLICIT NONE

! Arguments with intent (in):
CHARACTER (LEN = *), INTENT(IN) :: filename

! Arguments with intent(out):
TYPE (ObservationalNetwork), INTENT(OUT) :: network

!local declarations:
INTEGER (KIND = short) :: fileunit
INTEGER (KIND = short) :: err_io
INTEGER (KIND = short) :: i
CHARACTER (LEN = 300)  :: string
TYPE (IniList)         :: ini

!----------------------------end of declarations-------------------------------

!store path
network % path = filename


!open and read name value pairs name = value
CALL IniOpen (filename, ini)

!check and store network info
!description
IF (KeyIsPresent ('description', ini) ) THEN
    network % description = IniReadString ('description', ini)
ELSE !description is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'description missing in file: ', &
                argument = TRIM(filename) )
END IF

!unit
IF (KeyIsPresent ('unit', ini) ) THEN
    network % unit = IniReadString ('unit', ini)
ELSE !unit is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'unit missing in file: ', &
                argument = TRIM(filename) )
END IF

!epsg
IF (KeyIsPresent ('epsg', ini) ) THEN
    network % epsg = IniReadInt ('epsg', ini)
ELSE !epsg is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'epsg missing in file: ', &
                argument = TRIM(filename) )
END IF

!assign coordinate reference system from EPSG code
network % mapping = DecodeEPSG (network % epsg)

!number of stations
IF (KeyIsPresent ('count', ini) ) THEN
    network % countObs = IniReadInt ('count', ini)
ELSE !count is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'count missing in file: ', &
                argument = TRIM(filename) )
END IF

!dt
IF (KeyIsPresent ('dt', ini) ) THEN
    network % timeIncrement = IniReadInt ('dt', ini)
ELSE !dt is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'dt missing in file: ', &
                argument = TRIM(filename) )
END IF

!missing-data flag
IF (KeyIsPresent ('missing-data', ini) ) THEN
    network % nodata = IniReadReal ('missing-data', ini)
ELSE !missing-data is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'missing-data missing in file: ', &
                argument = TRIM(filename) )
END IF

!height offset
IF (KeyIsPresent ('offsetz', ini) ) THEN
    network % offsetZ = IniReadReal ('offsetz', ini)
ELSE !offsetz is missing
    CALL Catch ('error', 'ObservationalNetworks',   &
                'offsetz missing in file: ', &
                argument = TRIM(filename) )
END IF

!destroy ini
CALL IniClose (ini)

!open file
fileunit = GetUnit ()
OPEN (UNIT = fileunit, file = filename)

!scan for searching keyword "metadata"
string = ''
DO WHILE ( .NOT. (string(1:8) == 'metadata'))
!DO WHILE ( .NOT. (string(1:10) == 'anagrafica'))
	READ(fileunit,'(a)', iostat = err_io) string
	IF (err_io /= 0) THEN
	   CALL Catch ('error', 'ObservationalNetworks', &
       'keyword metadata not found in file: ',  &
       argument = TRIM(fileName) )     
    END IF
    string = StringCompact (string)
    string = StringToLower (string)
END DO

ALLOCATE (network % obs (network % countObs))

DO i = 1, network % countObs
	READ(fileunit,*) network % obs (i) % name, &
	                 network % obs (i) % id, &
	                 network % obs (i) % xyz % easting, &
	                 network % obs (i) % xyz % northing, &
	                 network % obs (i) % xyz % elevation
	!initialize observation values to nodata
	 network % obs (i) % value = network % nodata
END DO

CLOSE (fileunit)

RETURN
END SUBROUTINE ReadMetadataFileName